InitSpatialAverageSediment Subroutine

public subroutine InitSpatialAverageSediment(fileini, pathout, detrate)

Initialization of spatial average of sediment variables

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: fileini
character(len=*), intent(in) :: pathout
type(grid_real), intent(in) :: detrate

sediment detachment rate (kg/s)


Variables

Type Visibility Attributes Name Initial
type(IniList), public :: iniDB

Source Code

SUBROUTINE InitSpatialAverageSediment   & 
!
 (fileini, pathout, detrate)  

IMPLICIT NONE

!arguments with intent in:
CHARACTER(LEN = *), INTENT(IN)    :: fileini 
CHARACTER(LEN = *), INTENT(IN)    :: pathout     
TYPE (grid_real), INTENT(IN) :: detrate !!sediment detachment rate (kg/s)

!local declarations
TYPE(IniList)          :: iniDB
!-------------------------------end of declaration-----------------------------

!  open and read configuration file
CALL IniOpen (fileini, iniDB) 

! search for active variable for output
CALL Catch ('info', 'SpatialAverage', 'checking for sediment active variables ')

countsediment = 0

!detachment rate
IF ( IniReadInt ('detachment-rate', iniDB, section = 'sediment') == 1) THEN
   IF ( .NOT. ALLOCATED (detrate % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'detachment rate not allocated, &
                                            forced to not export spatial average ')
       sedimentout (1) = .FALSE.
   ELSE
       sedimentout (1) = .TRUE.
       countsediment = countsediment + 1
   END IF
ELSE
   sedimentout (1) = .FALSE.
END IF

sedimentInitialized = .TRUE.

CALL IniClose (iniDB) 

CALL ConfigureExtents (fileini, pathout)


RETURN
END SUBROUTINE InitSpatialAverageSediment